perm filename AM.ENG[TLK,DBL] blob sn#163801 filedate 1975-10-23 generic text, type C, neo UTF8
COMMENT ⊗   VALID 00004 PAGES
C REC  PAGE   DESCRIPTION
C00001 00001
C00002 00002	Description of the top level of control, and representation, in AM.
C00012 00003	 Some possibilities
C00018 00004	When space is tight, or in order to clean things up to make a file:
C00023 ENDMK
C⊗;
Description of the top level of control, and representation, in AM.

There are 3 basic Being functions:

GETB	(Getb B P) must fetch the contents of part P of Being B.
	An ancillary function is provided, GETBQ, whose arguments are quoted.
	Another version, SWGETB, is available for use when space is tight and
	there is some chance that B might be swapped out onto a disk file.
APPLYB	(Applyb B P A1 A2...) must execute the part P of Being B, with arguments
	bound to A1, A2,...
SETB	(Setb B P Q) must replace the contents of part P of Being B with Q.
	Notice that SETB must work properly if P is an executable part: 
	SETB may have to redefine B (e.g.), in order to ensure that APPLYB(B,P)
	will use the new code Q.
	An ancillary function is provided, SETBQ, whose arguments are quoted.
	Another version, SWSETB, is available for use when space is tight and
	there is some chance that B should soon be swapped out onto a disk file.
CREATEB	Createb(B) does whatever initialization is required to ensure that B
	will be treated as a BEING in the future, and that SETB, GETB, etc. will
	work properly on B.
SWAPB 	This swaps out an individual BEING onto a disk file, leaving behind a
	fairly efficient pointer for retrieving the (current) values of the parts.
GETU	(Getu B P) must fetch the value of the utility information stored under
	the category P of the BEING B. Such utility properties include:
	FROM-FILE, EXPR, CODE, CHANGED, FOUT.
PUTU	(Putu B P V) stores value V under utility property P on BEING B.


This is almost data-less programming (data-structure-independent).

Several secondary functions are defined in terms of these above primitives:

INCRB	(Incrb B P Q) adds the value Q to the existing value under part P of B.
DECRB	(Decrb B P Q) removes the value Q from the existing value under part P of B.
GC-B	This Garbage Collects by Swapb-ing BEINGs which haven't been used lately,
	destroying some records of long-past events, forgetting worthless BEINGs,...
RIPPLE	Ripple(B P) finds all existing entries under B.P↑n. That is, it appends
	B.P, B'.p for all B' ε B.p,  B''.p for all B'' in some B'.p....
RIPPLE-UNTIL	Ripple-until(B P PRED) ripples along until one of the BEINGs
	located satisfies the predicate PRED.
RIPPLE-SIMULT	Ripple-simult(B PLIST) is conceptually the same as 
	the union, for all p in PLIST, of Ripple(B p).
ACCEPT-B  This utility function accepts the name of a new BEING from the user,
	the name of an existing and similar BEING, makes the new BEING a copy of
	the old one, then asks the user to edit the new one to his satisfaction.
CHANGE-B  Given the name of a BEING and a part, this lets the user edit that part.



Finally, we note some very low-level functions, which are not explicitly mentioned
anywhere except within the definitions of the primitives above, and each other.

INIT-PART This low-level function, used by SETB and others, does all the necessary
	initialization so that B has a slot labelled P (unknown contents).
BPFS	Stands for Being Part/Function pairS. BPFS(B) is a low-level function
	which accesses the list of (<part-name> <code for retrieving the part>)
	pairs which each BEING has under the current representation.
NFACET  This utility function lets the user add a new kind of BEING PART to AM.
DEFP	Given a new part name, define it properly for the current represenation.
DEFB	Given a new BEING name, define it properly.
DWIMUSERFN	This is programmed to take care of swapping out the executable
	versions of BEINGs: an undefined function of the proper syntactic format
	is decoded, and the proper part of the proper BEING is accessed, compiled
	and then run.
GLUE!	Glue!(B P) is a command to pack B and P together into one name, and do
	whatever initialization is required to remember such a packing exists.
GLUE?	Glue?(B P) returns NIL if B has never been glued to P, else Glue!(B P).
GLUEE!	Glue together B and P into the name of the proper executable function for
	applying (executing) part P of BEING B. Initialize for GLUEE?, below.
GLUEE?	If B and P have ever been Gluee'ed, return that value, else return NIL.
PGET	A non-executable part is defined as a call on Pget. This function uses the
	CENT feature to guide rippling outward to locate all meaningful entries.
PXEQ	An executable part P is defined as a call like PXEQ(P B args), which
	executes part P of those BEINGs located in the CENT-guided rippling process.
PSUF	For parts which have ordered subparts to be interleaved. Similr to PXEQ.


The CENT feature:
	This is a nontrivial idea for locating related information.
First consider a particular situation: we want Examples of Relations.
Now clearly, any example of a specialization of the concept of Relation is
also an example of a Relation. (e.g., Examples of Functions are also examples
of Relations). In equation form, we could write EXS o SPEC ε EXS.
Many such equations turn out to be valid: here are a few of them:
SPEC o SPEC ε SPEC
GENL o GENL ε GENL
SPEC o EXS  ε EXS
EXS  o SPEC ε EXS
GENL o UP   ε UP
FILLIN o GENL ε FILLIN
CHECK  o GENL ε CHECK

There seem to be two basic formats for these equations:
1) P o q ε P
2) q o P ε P

So in order to collect the entries belonging under part P of BEING B,
we should really access not just B.P, but also (B.q).P for all q in category 1,
and also (B.P).q for all q in category 2.

Notice that all the equations are implictly "∀B...", so that the sets q↓1, q↓2
depend only upon which part P we are interested in. 

In AM, then, we have two lists CENT1 and CENT2, associated with each part P.
To access all entries of a part of a BEING, we access that part of that BEING,
plus all the associated slots indicated by the CENT lists of that part-name.
In fact, we define, e.g., (GENL  B) as the union of (Getb B 'Genl) with
the union of (Genl B') for all B'ε CENT1(GENL), unioned with the union of
(Getb B' P') for all P' on CENT2(GENL), and all B' on (Genl B).
This is explosively recursive, primarily because of the CENT2 list.
For efficiency, we limit CENT2 lists, and terminate our search after a certain
CPU time expenditure, or after finding a certain number of entries.



 Some possibilities
for the 3 functions are:

1. GETB ≡ GET		Part name/value pairs stored as the value of B.
   SETB ≡ PUTL
   APPLYB ≡ (λ (B P A1...) (Apply* (Getb B P) A1...))

2. GETB ≡ GETP		Part name/value pairs stored on the property list of B.
   SETB ≡ PUT
   APPLYB ≡ (λ (B P A1...) (Apply* (List 'λ (Gethash P Args) (Getb B P)) A1...))

3. GETB ≡ (λ (B P BP) 
		(Setq BP (Glue B P))
		(Cond 	((Getd BP) (Apply* BP))
			((And (Loadfns BP (Getp BP 'From-file))
			      (Getd BP)
			      (Apply* BP]
   
   SETB ≡ [λ (B P Q) 
		(Setq BP (Glue B P))
		(Putd BP (List 'λ (Gethash P Args) Q]

   APPLYB ≡ (λ (B P) (Getb B (Pack (List 'C- P))))

   where Glue can be, e.g., (Pack (List B '- P)), or 
			    (Gethash B (Eval P)) which uses up the parts' value cells.
   where each part of each BEING is treated as a function in its own right.

4. GETB ≡ (λ (B P BP) 
		(Setq BP (Glue B P))
		(Cond 	((Neq (Car BP) 'Nobind)  BP)
			((And (Loadvars BP (Getp B 'From-file))
			      (Neq (Car BP) 'Nobind)
			      BP]
   
   SETB ≡ [λ (B P Q) 
		(Set (Glue B P) Q]

   APPLYB ≡ (λ (B P BP) 
		(Setq BP (Gluec B P))
		(Cond 	((Neq (Car BP) 'Nobind)  BP)
			((And (Loadvars BP (Getp B 'From-file))
			      (Neq (Car BP) 'Nobind)
			      BP]
   
   where Glue can be, e.g., (Pack (List B '- P)), or 
			    (Gethash B (Eval P)).
   where Gluec can be (Pack (List B '-C- P)), or (Gethash B (Eval (Gethash P prec))),
		or, more generally, (Glue B (Glue 'C P)).

   where each part of each BEING is treated as a variable in its own right.


5. GETB ≡ APPLY*

   SETB ≡ (λ (B P Q bold cp)
		(Cond ((Nlistp (Getd B))
		        (Setq bold (Pack (List B '-old)))
			(Movd B bold T)
			(Putd B (Subst B 'bname trivb))))
	      	(Attach (List P (Allq Q)) (PVS B)))
		(Cond ((Setq cp (Gethash P prec))
			(Attach (List cp Q) (PVS B]

   APPLYB ≡ (λ (B P) (Getb B (Prec P)))

   where Prec can be (Pack (List '-C- P)), or (Gethash P Prec),
		or, more generally, (Glue  'C P)).

   where PVS accesses the (part-name part-value) pairs in the defn of the Being,
	so we might define PVS as (λ (B) (CDDR (CADDR (GETD B)))).

   this scheme has each Being be a big selectq, with keys as part names.


6. GETB ≡ GET		Part name/value pairs stored as the value of B.
   SETB ≡ (λ (B P Q  bold  pv pvl)
		(Putl B P Q)
		(Cond ((Gethash P prec)
			(Cond ((Nlistp (Getd B))
			        (Setq bold (Pack (List B '-old)))
				(Movd B bold T)
				(Putd B (Subst B 'bname trivb))))
			(Cond ((Setq pv (assoc P (Setq pvl (PVS B)))
				(Rplacd pv (list Q)))
			      (T (Attach (List P Q) pvl]
		
   APPLYB ≡ APPLY*


7. GETB ≡ GETP		Part name/value pairs stored as the value of B.
   SETB ≡ (λ (B P Q  bold  cp)
		(Put B P Q)
		(Cond ((Setq cp (Gethash P prec))
			(Cond ((Nlistp (Getd B))
			        (Setq bold (Pack (List B '-old)))
				(Movd B bold T)
				(Putd B (Subst B 'bname trivb))))
		        (Attach (List cp Q) (PVS B]
		
   APPLYB ≡ (λ (B P A1...) (Apply* B (Gethash P prec) A1...))


8. GETB ≡ GET		Part name/value pairs stored as the value of B.
   SETB ≡ (λ (B P Q)
		(Putl B P Q)
		(Cond ((Gethash P prec)
			(Set-compile1-flags)
			(Compile1 (Cond ((Gethash B P))
	  		                (T (Puthash B P (Pack (List B '- P)))))
			          (List 'λ (Gethash P args) Q]
				
   APPLYB ≡ (λ (B P A...)  (Apply* (Gethash B P) A...))

   So each executable part is a separate function.

When space is tight, or in order to clean things up to make a file:

CONDENSEB	This takes a Being and merges all its fixups into it.

For example, for #6 on the last page, we could define

Condenseb (λ (B pvl1 pvl2 pvl3)
		(Cond ((Nlistp (Getd B)) T)
		      (T 
			(Setq pvl1 (PVS B))
			(Loadfns B (Getp B 'from-file) T)(discard old defn)
			(Setq pvl2 (PVS B))
			(Mapc pvl1 (Function (λ (pv)
					(Cond ((Setq pvl3 (Assoc (Car pv) pvl2))
						(Rplacd pvl3 (Cdr pv)))
					      (T 
						(Attach pv pvl2)))
			    )))
		))
	)


For #6, we would Dreverse pvl1 when we get it, and probably lop off the Car as well.

The actual dumping, for making a file, could be handled by COMS
(in the proper fileCOMS variable). For #6 on the last page, we would want to
save all properties of a BEING, its value, and its definition.

Most of the hash table contents, etc. can be done by an initialization routine.

Finally, we need to plan out in advance how we would convert from one representation
to another (perhaps one not even thought of yet). Clearly, we must redefine
Getb, Setb, Applyb, and probably Condenseb.
Notice that none of the contents of any of the Beings' parts would need modification:
Since they only involve calls on Getb,..., they never notice that the representation
has changed. What we would have to do, though, is transform the place/manner in
which those parts are stored. For example, to convert between #6-#7 requires
only that we redefine the four manipulation functions. To convert from
#1 to #7 entails this redefinition, and also RPLACD-ing the Being with itself (to
transfer its part/value pairs from the value cell to the property list), and finally
mapping along the list of BEINGs, defining each one as a selectq, with just those
entries (cp q), where p is executable and (p q) now appears on the prop. list of B.

A more general scheme for this process might be phrased:
	i) redefine Getb, Setb, Applyb, Condenseb, PVS	as required
       ii) use old-Getb to map along the parts of the existing structure of a BEING,
	   and for each part so accessed, use the new-Setb to properly relocate it.
      iii) condense each Being, using the new-Condenseb.


Step (ii) should be prefaced by Createb(B), to initialize a new Being structure;
perhaps this should be preceded by a Saveb(B), which sets the variables
save-exs, save-contents, save-algs,... to the appropriate part values. This is
in case Create (or Setb) might reuse the same structures that B used originally.

Saveb(B) can always be defined as mapping along Facets, assigning the associated
	variable to a copy of the result of Getb-ing that part of B.

Createb(B) might have to be redefined when representation changes. One might
	define B as a trivial sort of Selectq, with only a bottom case clause, e.g.
	for #6, but not treat B as a function at all for other representations
	(like #1). So there are really 6 functions to worry about each time:
	Getb, Setb, Applyb, PVS, Condenseb, and Createb.